home *** CD-ROM | disk | FTP | other *** search
/ Language/OS - Multiplatform Resource Library / LANGUAGE OS.iso / prolog / swi-prol / edit.pl < prev    next >
Text File  |  1994-07-10  |  5KB  |  191 lines

  1. /*  $Id: edit.pl,v 1.3 1993/02/17 12:45:46 jan Exp $
  2.  
  3.     Copyright (c) 1990 Jan Wielemaker. All rights reserved.
  4.     jan@swi.psy.uva.nl
  5.  
  6.     Purpose: editor interface
  7. */
  8.  
  9. :- module($edit,
  10.     [ edit/1
  11.     , edit/0
  12.     , ed/1
  13.     , ed/0
  14.     , make/0
  15.     ]).
  16.  
  17. :- user:dynamic
  18.     edit_source/1.
  19. :- user:multifile
  20.     edit_source/1.
  21.  
  22. :- module_transparent
  23.     edit/1, 
  24.     ed/1.
  25.  
  26. edit(File) :-
  27.     $break($check_file(File, _)), !, 
  28.     $record_last($edit_file, File), 
  29.     $edit_load(File).
  30. edit(File) :-
  31.     $confirm('Edit new file ~w', [File]),
  32.     $record_last($edit_file, File), 
  33.     $edit(File).
  34.  
  35. edit :-
  36.     recorded($edit_file, File), 
  37.     $confirm('Edit file `~w''', [File]), !,
  38.     edit(File).
  39.  
  40. ed(Spec) :-
  41.     $find_predicate(Spec, Preds),
  42.     (   Preds = [Head]
  43.     ;   member(Head, Preds), 
  44.         $predicate_name(Head, PredName),
  45.         $confirm('Edit predicate `~w''', [PredName])
  46.     ), !, 
  47.     source_file(Head, File), 
  48.     predicate_property(Head, line_count(LineNo)),
  49.     $strip_module(Head, Module, Term), 
  50.     functor(Term, Name, Arity), 
  51.     $record_last($edit_predicate, Module:Name/Arity), 
  52.     $edit_load(File:LineNo:Name/Arity).
  53.  
  54. ed :-
  55.     $module(TypeIn, TypeIn), 
  56.     recorded($edit_predicate, TypeIn:Name/Arity), !, 
  57.     $confirm('Edit predicate `~w/~w''', [Name, Arity]), !, 
  58.     ed(TypeIn:Name/Arity).
  59. ed :-
  60.     recorded($edit_predicate, Module:Name/Arity), !, 
  61.     $confirm('Edit predicate `~w:~w/~w''', [Module, Name, Arity]), !, 
  62.     ed(Module:Name/Arity).
  63. ed :-
  64.     $break($warning('ed/0: You can only use ed/0 after ed/1!')).
  65.  
  66. $record_last(Key, Term) :-
  67.     recorded(Key, Last) -> 
  68.     Last = Term, !.
  69. $record_last(Key, Term) :-
  70.     recorda(Key, Term).
  71.  
  72. $edit_load(File:Predicate) :-
  73.     $check_file(File, Path), 
  74.     $edit(Path:Predicate), !.
  75. $edit_load(File) :-
  76.     File \= _:_,
  77.     $check_file(File, Path), 
  78.     $edit(Path), !.
  79. $edit_load(_, _).
  80.  
  81. $edit(Spec) :-
  82.     user:edit_source(Spec), !.
  83. $edit(File:LineNo:Name/_Arity) :- !,
  84.     (   (   getenv('EDITOR', Editor)
  85.         ;   $default_editor(Editor)
  86.         )
  87.     ->  (    (   edit_command(Editor, File, LineNo, Name, Command)
  88.         ;   edit_command(Editor, File, LineNo, $nopredicate, Command)
  89.         )
  90.         ->  shell(Command),
  91.         make
  92.         )
  93.     ).
  94. $edit(File) :-
  95.     (   (   getenv('EDITOR', Editor)
  96.         ;   $default_editor(Editor)
  97.         )
  98.     ->  edit_command(Editor, File, 1, $nopredicate, Command),
  99.         shell(Command),
  100.         make
  101.     ).
  102.  
  103. edit_command(Editor, File, _Line, $nopredicate, Command) :- !,
  104.     $file_base_name(Editor, Base),
  105.     (   edit_command(Base, nosearch, Cmd)
  106.     ->  name(Cmd, S0),
  107.         substitute("%e", Editor, S0, S1),
  108.         substitute("%f", File, S1, S),
  109.         name(Command, S)
  110.     ;   $warning('Don''t know how to use editor `~w''', [Editor])
  111.     ).
  112. edit_command(Editor, File, Line, Pred, Command) :-
  113.     $file_base_name(Editor, Base),
  114.     (   edit_command(Base, search, Cmd)
  115.     ->  name(Cmd, S0),
  116.         substitute("%e", Editor, S0, S1),
  117.         substitute("%f", File, S1, S2),
  118.         substitute("%s", Pred, S2, S3),
  119.         substitute("%d", Line, S3, S),
  120.         name(Command, S)
  121.     ).
  122.  
  123. /* - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
  124. edit_command(+Editor, +search, -Command)
  125.  
  126. This predicate should specify the  shell-command   called  to invoke the
  127. user's editor.  The following substitutions will be made:
  128.  
  129.     %e        Path name of the editor
  130.     %f        Path name of the file to be edited
  131.     %s        Name of the predicate (only for `search')
  132.     %d        Line number of the predicate (only for `search')
  133.  
  134. To locate a predicate in  a   source-file,  two mechanisms are provided.
  135. The first will *search* for the   predicate definition, while the second
  136. uses the *line-number* info from the Prolog system.  Searching generally
  137. only handles finding the  definition  of   the  first  occurrence of the
  138. predicate, disregarding the arity information.    Using  line-numbers is
  139. not sensitive to changes.  Smart editors  may pass both informations and
  140. search nearby the given line number.
  141. - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - */
  142.  
  143. edit_command(top,   search,   '%e ''%f'' ''-^%s''').
  144. edit_command(vi,    search,   '%e ''+/^%s'' ''%f''').
  145. edit_command(emacs, search,   '%e +%d ''%f''').
  146. edit_command(_,     nosearch, '%e ''%f''').
  147.  
  148. substitute(From, ToAtom, Old, New) :-
  149.     name(ToAtom, To),
  150.     append(Pre, S0, Old),
  151.     append(From, Post, S0) ->
  152.     append(Pre, To, S1),
  153.     append(S1, Post, New), !.
  154. substitute(_, _, Old, Old).
  155.  
  156.  
  157.         /********************************
  158.         *              MAKE             *
  159.         *********************************/
  160.  
  161. %    make
  162. %    Reload all source files that have been changed since they were
  163. %    loaded.
  164.  
  165. make :-
  166.     $update_library_index,
  167.     $time_source_file(File, LoadTime),
  168.     time_file(File, Modified),
  169.     Modified @> LoadTime,
  170.     reload(File),
  171.     fail.
  172. make.
  173.  
  174.  
  175. %    reload(File)
  176. %
  177. %    Reload file in proper module.  Note that if the file is loaded
  178. %    into multiple modules this should be handled more carefully.
  179.  
  180. reload(File) :-
  181.     findall(Context, $load_context_module(File, Context), Modules),
  182.     (   Modules = []
  183.     ->  consult(user:File)
  184.     ;   Modules = [Module]
  185.     ->  consult(Module:File)
  186.     ;   Modules = [First|_Rest],
  187.         consult(First:File)
  188.     ).
  189.     ).
  190.     
  191.